home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Cream of the Crop 1
/
Cream of the Crop 1.iso
/
MONITOR
/
TXTCAP20.ARJ
/
TEXTCAP.ASM
< prev
next >
Wrap
Assembly Source File
|
1991-12-05
|
41KB
|
864 lines
;----------------------------------------------------------------------
; TEXTCAP is a resident utility which copies a text screen
; to a file. Activate TEXTCAP by pressing Ctrl-F9 or the hot key
; specified by /K<number> on the command line. Help by /?.
; The filename will be SCNxxxxx.TXT. The number part begins with 00000
; and is incremented by 1 each time TEXTCAP is activated.
; ---> Authored originally by Tom Kihlken for PC Magazine in 1987 <---
; ---> Heavily modified by TapirSoft Gisbert W.Selke, 04 Dec 1991 <---
; amongst others a mini-API via INT 16h, ax=4252h..4254h:
; 4252h : installation check, responds with 5242h
; 4253h : removal from memory, responds with segment we used; calling programme
; must de-allocate this segment!
; 4254h : dump text screen now, responds with 5442h
;-----------------------------------------------------------------------
;-----------------------------------------------------------------------
BIOS_SEG SEGMENT AT 0040H
ORG 0017H
KB_FLAG DB ? ;BIOS keyboard shift status
BIOS_SEG ENDS
;=======================================================================
CSEG SEGMENT
Assume CS:CSEG, DS:CSEG, ES:CSEG
Org 0080h
CmdLine Label Byte ; pointer to command line
ORG 0100H ; Beginning for .COM programs
START: JMP INITIALIZE ; Initialization code is at end
;-----------------------------------------------------------------------
; Data needed by this program
;-----------------------------------------------------------------------
NROWS Equ 50 ; max number of lines on screen
NCOLS Equ 132 ; max number of columns per line
NBYTES Equ NROWS*NCOLS*2 ; length of screen in bytes
DosCall Equ 21h ; DOS interrupt number
PrintChar Equ 02h ; DOS function 'print char'
PrintString Equ 09h ; DOS function 'print string'
SetVec Equ 2500h ; DOS function 'set interrupt vector'
Keep Equ 3100h ; DOS function 'stay resident'
GetVec Equ 3500h ; DOS function 'get interrupt vector'
FreeMem Equ 49h ; DOS function 'free memory'
Exec Equ 4Bh ; DOS function 'exec'
ExitCode Equ 4Ch ; exit with error code
ChkCode Equ 4252h ; our special installation check
RemoveCode Equ 4253h ; our special request for removal
DumpCode Equ 4254h ; our special request for dumps
InstalledCode Equ 5242h ; footprint 'installed'
Tab Equ 09h ; ASCII tab
CR Equ 0Dh ; carriage return
LF Equ 0Ah ; line feed
CtrlZ Equ 1Ah ; end-of-file mark
CopyRight db CR, 'TEXTCAP 2.0 (c) 1987/91 Ziff Communications Co'
db '/TapirSoft Gisbert W.Selke$', CtrlZ
FileName db 80 Dup (0) ; output path and file name
FileNamePtr dw FileName ; pointer to beginning etc.
HotKey db 43h ; scan code of F9
ShiftMask db 00000100b ; shift mask: any Ctrl key
OldInt09 DD ? ;Old hardware keyboard interrupt vector
OldInt13 DD ? ;Old BIOS disk I/O interrupt vector
OldInt16 DD ? ;Old keyboard input interrupt vector
OldInt21 DD ? ;Old DOS function interrupt vector
CRT_MODE DB ? ;Current video mode
CRT_ROWS DB ? ;Number of lines on screen
CRT_COLS DB ? ;Number of columns on screen, possibly adjusted
CRT_SIZE DW ? ;Actual screen size in bytes (chars+attributes)
ACTIVE_PAGE DB ? ;Number of active video page
WriteFile DB 0 ;If=1, need to write to disk
ACTIVE DB 0 ;Indicates CAPTURE is in use
DOS_Stat DB 0 ;Current DOS function indicator
Busy_flags DB 0 ;Bit masked as follows:
; 1 - DOS function is active
; 2 - BIOS disk I/O is active
;-----------------------------------------------------------------------
; CAPTURE reads the screen and stores it in an internal buffer.
;-----------------------------------------------------------------------
CAPTURE PROC NEAR
Assume DS:CSEG, ES:BIOS_SEG
MOV AH, 0Fh ;Get current video mode
INT 10h
MOV CRT_COLS, AH ;Store number of screen columns
MOV CRT_MODE, AL ;Store video mode
MOV ACTIVE_PAGE, BH ;Store video page
XCHG AH, AL ;Number of columns in AL
XOR AH, AH
CMP AX, NCOLS ;Compare to maximum; may be > 127!
JBE SAVE_COLS ;Skip if we can handle it
MOV AL, NCOLS ;Else use adjusted number
SAVE_COLS: MOV CRT_COLS, AL ;Store in CRT_COLS
PUSH AX ;Save for a sec
MOV DL, 25d ;Default number of lines
MOV AL, CRT_MODE ;Get video mode
CMP AL, 07h ;If 80*25 text, then ok
JE SET_SIZE
MOV AX, 1130h ;Else try to get max line
INT 10h ; ... in DL
INC DL ;Adjust to get # lines
CMP DL, NROWS ;at most NROWS allowed!
JBE SET_SIZE
MOV DL, NROWS
SET_SIZE:
MOV CRT_ROWS, DL ;Jot down # lines
POP AX ;Get back number of columns
MUL DL ;Multiply to get #chars on screen
SHL AX, 1 ;Double for chars+attributes
MOV CRT_SIZE, AX ;This many bytes to write!
MOV AH, 03h ;Cursor pos for this page
MOV BH, ACTIVE_PAGE
INT 10h
PUSH DX ;Save the cursor location
MOV DI,OFFSET BUFFER ;DS:DI points to the buffer
XOR DX,DX ;Start at row 0, column 0
READ_LOOP:
MOV AH, 02h
MOV BH, ACTIVE_PAGE
INT 10h ;Tell BIOS where the cursor is
MOV BH,ACTIVE_PAGE ;Get active page from BIOS data
MOV AH,8 ;BIOS function to read character
INT 10H ;Read the character/attribute
MOV [DI],AX ;Put the character in buffer
INC DI ;Increment the pointer twice
INC DI ;Since we stored a word
INC DL ;Do the next char in same row
CMP DL,DS:CRT_COLS ;At the right border yet?
JNE READ_LOOP ;Do all characters in this row
INC DH ;Move to next row
XOR DL,DL ;Back to left edge (Column 0)
CMP DH,DS:CRT_ROWS ;Done all rows yet?
JNE READ_LOOP ;Loop until whole screen is read
MOV AH, 02h ;Cursor pos for this page
MOV BH, ACTIVE_PAGE
POP DX
INT 10h ;Recover the cursor position
RET ;Then were finished
CAPTURE ENDP
;-----------------------------------------------------------------------
; This copies the buffer contents to a file. It should only be called
; when DOS is in a stable and reentrant condition.
;-----------------------------------------------------------------------
WRITE_TO_FILE PROC NEAR
Assume DS:NOTHING, ES:NOTHING
MOV WriteFile,0 ;Turn off request flag
STI ;Get interrupts back on
PUSH AX ;Must preserve all registers
PUSH BX
PUSH CX
PUSH DX
PUSH BP
PUSH DS
PUSH ES
PUSH CS
POP DS
Assume DS:CSEG ;DS points to our code segment
MOV AX,3524H ;Get DOS critical error vector
CALL DOS_FUNCTION ;Do the DOS function
PUSH BX ;Save old INT 24 vector on stack
PUSH ES
; Replace the DOS severe error interrupt with our own routine.
MOV DX,OFFSET NEWINT24
MOV AX,2524H ;Setup to change INT 24h vector
CALL DOS_FUNCTION ;DOS function to change vector
; Try to open the file to determine if it already exists. If it does,
; then just close it and increment the filename.
OPEN_FILE: MOV DX,OFFSET FILENAME ;DS:DX points to filename
MOV AX,3D00H ;Open file for read access
CALL DOS_FUNCTION ;Do the DOS function
JC OPEN_ERROR ;If open error, take jump
MOV BX,AX ;Need the handle in BX
MOV AH,3EH ;Close this file
CALL DOS_FUNCTION ;Do the DOS function
CALL INC_FILENAME ;Try the next filename
JMP OPEN_FILE
OPEN_ERROR:
CMP AX,2 ;Was it 'file not found' error?
JNE DOS_ERR_EXIT ;Exit on any other error
; Now create the file, then write buffer contents and close it.
MOV DX,OFFSET FILENAME ;DS:DX points to filename
MOV CX,0020H ;Attribute for new file
MOV AH,3CH ;Create file for writing
CALL DOS_FUNCTION ;Do the DOS function
JC CLOSE_FILE ;On any error, take jump
MOV BX,AX ;Save handle in BX
MOV DX,OFFSET BUFFER;Point to output buffer
MOV CX,DS:CRT_SIZE ;Write correct number of bytes
MOV AH,40H ;DOS 'write to a device' function
CALL DOS_FUNCTION ;Do the DOS function
CLOSE_FILE:
MOV AH,3EH ;DOS function to close the file
CALL DOS_FUNCTION ;Do the DOS function
CALL INC_FILENAME ;Move to next filename
DOS_ERR_EXIT: POP DS ;Get INT 24H vector from stack
Assume DS:NOTHING
POP DX
MOV AX,2524H ;Restore critical error vector
CALL DOS_FUNCTION ;Do the DOS function
POP ES ;Finally restore all registers
POP DS
POP BP
POP DX
POP CX
POP BX
POP AX
MOV ACTIVE,0 ;CAPTURE is done now
RET ;Finished writing to disk
WRITE_TO_FILE ENDP
;-----------------------------------------------------------------------
; This routine does a dos function by calling the old interrupt vector
;-----------------------------------------------------------------------
Assume DS:NOTHING, ES:NOTHING
DOS_FUNCTION PROC NEAR
PUSHF ;These instructions simulate
CLI ;an interrupt
CALL CS:OldInt21 ;Do the DOS function
STI
RET
DOS_FUNCTION ENDP
;-----------------------------------------------------------------------
; This procedure increments the number part of the filename.
;-----------------------------------------------------------------------
INC_FILENAME PROC NEAR
MOV BX, FileNamePtr ;Point to last digit
INC_NEXT_CHAR:
INC BYTE PTR [BX] ;Increment the extension
CMP BYTE PTR [BX],"9" ;Check for carry
JLE INC_RETURN ;If none, we're finished
MOV BYTE PTR [BX],"0" ;Set this digit to zero
DEC BX ;Backup to next digit
CMP BX,OFFSET FILENAME+2 ;increment digits only
JLE INC_RETURN
JMP INC_NEXT_CHAR
INC_RETURN:
RET
INC_FILENAME ENDP
;-----------------------------------------------------------------------
; Interrupt 09 (Keyboard) Watch for trigger key. When found, ignore
; it and execute the CAPTURE routine.
;-----------------------------------------------------------------------
NEWINT09 PROC FAR
Assume DS:NOTHING, ES:NOTHING
STI ;Allow other interrupts
PUSH AX ;Must save processor state
IN AL,60H ;Get the scan code
CMP AL,HOTKEY ;Is it the hot key?
JE TRIGGER ;If yes, check the mask
INT09_EXIT: POP AX ;Restore the processor state
JMP CS:OldInt09 ;Continue with ROM routine
TRIGGER:
PUSH DS ;Preserve DS register
MOV AX,BIOS_SEG ;Get BIOS data segment
MOV DS,AX ;Put it in a segment register
Assume DS:BIOS_SEG
MOV AL,KB_FLAG ;Shift flags
AND AL,0FH ; only
CMP AL,ShiftMask ;Is the ALT key down?
POP DS ;Restore DS register
Assume DS:NOTHING
JNE INT09_EXIT ;If ALT not down, ignore it
;Reset the keyboard and 8259 interrupt controller
IN AL,61H
MOV AH,AL
OR AL,80H ;Reset bit for keyboard
OUT 61H,AL ;Reset the keyboard
MOV AL,AH
JMP SHORT $+2 ;A short delay
OUT 61H,AL ;Reenable keyboard
CLI
MOV AL,20H
OUT 20H,AL ;Reset interrupt controller
STI
CMP ACTIVE,0 ;Is CAPTURE already active?
JNZ SHORT_RET ;If active, then exit
MOV ACTIVE,1 ;It's active now!
PUSH BX ;Must preserve all registers
PUSH CX
PUSH DX
PUSH BP
PUSH DI
PUSH DS
PUSH ES
PUSH CS
POP DS ;Set DS to CSEG
MOV AX,BIOS_SEG ;ES points to BIOS data area
MOV ES,AX
Assume DS:CSEG, ES:BIOS_SEG ;Assembler directives
CALL CAPTURE ;Read the screen contents
MOV WriteFile,1 ;Indicate need to flush buffer
POP ES ;Restore all registers
POP DS
POP DI
POP BP
POP DX
POP CX
POP BX
Assume DS:NOTHING, ES:NOTHING
TEST Busy_flags,011B ;Is DOS or BIOS disk busy?
JNZ SHORT_RET ;If yes, then we must wait
CALL WRITE_TO_FILE ;Otherwise, we'll do it now
SHORT_RET:
POP AX ;Stack must be restored
IRET ;Now we're all done
NEWINT09 ENDP
;-----------------------------------------------------------------------
; Interrupt 13H (BIOS diskette I/O) Set the busy flag during diskette I/O
;-----------------------------------------------------------------------
NEWINT13 PROC FAR
Assume DS:NOTHING, ES:NOTHING
PUSHF
OR CS:Busy_flags,010B ;Set BIOS busy bit
POPF
PUSHF ;This simulates an interrupt
CALL CS:OldInt13 ;Do the BIOS function
PUSHF ;Save result flags
AND Busy_flags,11111101B ;Clear BIOS busy bit
POPF ;Get back result flags
STI ;Must return with interrupts on
RET 2 ;Return BIOS result flags
NEWINT13 ENDP
;-----------------------------------------------------------------------
; Interrupt 16H (BIOS keyboard interface) Check to see if the buffer
; needs to be written.
;-----------------------------------------------------------------------
NEWINT16 PROC FAR
Assume DS:NOTHING, ES:NOTHING
Cmp ax, ChkCode ; is it 'are you there?' ?
Jne NI16A
NI16AA: XChg ah, al ; if so, tell we are indeed!
IRet
NI16A: Cmp ax, DumpCode ; should we dump a screen?
Jne NI16B
PUSH AX ;Must preserve all registers
PUSH BX
PUSH CX
PUSH DX
PUSH BP
PUSH DI
PUSH DS
PUSH ES
PUSH CS
POP DS ;Set DS to CSEG
MOV AX,BIOS_SEG ;ES points to BIOS data area
MOV ES,AX
Assume DS:CSEG, ES:BIOS_SEG ;Assembler directives
CALL CAPTURE ;Read the screen contents
MOV WriteFile,1 ;Indicate need to flush buffer
POP ES ;Restore all registers
POP DS
POP DI
POP BP
POP DX
POP CX
POP BX
POP AX
Assume DS:NOTHING, ES:NOTHING
TEST Busy_flags,011B ;Is DOS or BIOS disk busy?
JNZ SHORT_RET ;If yes, then we must wait
CALL WRITE_TO_FILE ;Otherwise, we'll do it now
Jmp Short NI16AA
NI16B: Cmp ax, RemoveCode ; should we remove ourselves?
Je NI16Remove ; if so, that's ok with us
CMP CS:WriteFile,1 ;Anything to write to disk?
JE CHECK_DOS_Stat ;If yes, see what DOS is doing
BIOS_KB:
JMP CS:OldInt16 ;Just do normal KB routine
CHECK_DOS_Stat:
CMP CS:DOS_Stat,0AH ;Doing read string?
JE BEGIN_NOW ;If yes, it's safe to begin
CMP CS:DOS_Stat,08H ;Doing keyboard input?
JNE BIOS_KB ;If yes, it's safe to begin
BEGIN_NOW:
CALL WRITE_TO_FILE ;Write the buffer to disk
OR CS:Busy_flags,001B ;Reset DOS busy bit
JMP CS:BIOS_KB ;Continue with BIOS routine
NI16Remove: Mov dx, word ptr [cs:OldInt09]; otherwise start removal
Mov ax, word ptr [cs:OldInt09+2]
Mov ds, ax
Mov ax, SetVec+09h ; Reestablish old INT 09h handler
Int DOSCall
Mov dx, word ptr [cs:OldInt13]
Mov ax, word ptr [cs:OldInt13+2]
Mov ds, ax
Mov ax, SetVec+13h ; Reestablish old INT 13h handler
Int DOSCall
Mov dx, word ptr [cs:OldInt16]
Mov ax, word ptr [cs:OldInt16+2]
Mov ds, ax
Mov ax, SetVec+16h ; Reestablish old INT 16h handler
Int DOSCall
Mov dx, word ptr [cs:OldInt21]
Mov ax, word ptr [cs:OldInt21+2]
Mov ds, ax
Mov ax, SetVec+21h ; Reestablish old INT 16h handler
Int DOSCall
Mov ax, cs ; Return our segment
IRet
NEWINT16 ENDP
;-----------------------------------------------------------------------
; Interrupt 21H (DOS functions) Used to keep track of DOS function calls
;-----------------------------------------------------------------------
NEWINT21 PROC FAR
Assume DS:NOTHING, ES:NOTHING
PUSHF ;Save the flags
MOV CS:DOS_Stat,AH ;Store the function number
OR CS:Busy_flags,001B ;Set DOS busy bit
OR AH,AH ;Doing function zero?
JZ JUMP_TO_DOS ;If yes, take the jump
CMP AH, Exec ;Doing EXEC function?
JE JUMP_TO_DOS ;If yes, take the jump
POPF
PUSHF
CALL CS:OldInt21 ;Do the DOS function
PUSHF ;Save the result flags
AND CS:Busy_flags,11111110B ;Clear DOS busy bit
CMP CS:WriteFile,1 ;Anything to write to disk?
JNE NO_WRITE ;If not, just return
CALL WRITE_TO_FILE ;Safe to access disk now
NO_WRITE:
POPF ;Recover DOS result flags
STI ;Must return with interrupts on
RET 2 ;Return with DOS result flags
JUMP_TO_DOS:
POPF
JMP CS:OldInt21
NEWINT21 ENDP
;-----------------------------------------------------------------------
; Interrupt 24H (critical DOS error). This interrupt is only in
; effect during a write screen. It is required to suppress the
; 'Abort, Retry, Ignore' message. All fatal disk errors are ignored.
;-----------------------------------------------------------------------
NEWINT24 PROC FAR
Assume DS:NOTHING, ES:NOTHING
XOR AL,AL ;Tells DOS to ignore the error
IRET ;That's all we do here
NEWINT24 ENDP
;----------------------------------------------------------------------
; This area is overwritten by the dynamic buffers.
;----------------------------------------------------------------------
PC = $
BUFFER = PC
PC = PC+NBYTES
LASTBYTE = PC
;-----------------------------------------------------------------------
; Here is the code used to initialize HerCap. It is not kept resident.
; The buffer is located here and overlays the initialization code.
;-----------------------------------------------------------------------
Assume CS:CSEG, DS:CSEG, ES:NOTHING
INITIALIZE PROC NEAR
MOV DX,OFFSET CopyRight
MOV AH, PrintString ;DOS display string service
INT DosCall ;Display title message
Call ParseArgs ; check command line parameters
; ah has function code:
Cmp ah, 1 ; request for help?
Jne Init2 ; if not, proceed to check
Mov dx, Offset Usage; usage text
Mov al, 1 ; exit code
ShowMsg: Push ax
Mov ah, PrintString
Int DosCall
Pop ax
mov ah, ExitCode ; exit with error code set earlier
int DosCall
; Search for a previously installed copy of CAPTURE
Init2: Cmp ah, 3 ; request for key help?
Jne Init2A
Jmp ShowKey ; if so, do it
Init2A: Mov bx, ax
Mov ax, ChkCode ; now check if we're loaded
Int 16h ; already loaded <-> ax = 0
Cmp bh, 2 ; request for removal?
Jne Init2B
Jmp Remove ; proceed to remove
; now we should install;
Init2B: Cmp ax, InstalledCode ; are we there already?
Jne Init3 ; if not, proceed normally
Mov dx, Offset LoadedMsg ; tell we're already there
Mov al, 2 ; error code 2
Jmp Short ShowMsg ; and exit to DOS
Init3: MOV AX,GetVec+09h ;Get keyboard break vector
INT DosCall
MOV WORD PTR [OldInt09], BX ;Save segment
MOV WORD PTR [OldInt09+2],ES ;Save offset
MOV DX, OFFSET NEWINT09
MOV AX, SetVec+09h
INT DosCall ;DOS function to change vector
MOV AX,GetVec+13h ;Get BIOS disk interrupt vector
INT DosCall
MOV WORD PTR [OldInt13], BX ;Save the segment
MOV WORD PTR [OldInt13+2],ES ;Save the offset
MOV DX, OFFSET NEWINT13
MOV AX, SetVec+13h
INT DosCall ;DOS function to change vector
MOV AX,GetVec + 16h ;Get keyboard input vector
INT DosCall
MOV WORD PTR [OldInt16], BX ;Save the segment
MOV WORD PTR [OldInt16+2],ES ;Save the offset
MOV DX, OFFSET NEWINT16
MOV AX, SetVec + 16h
INT DosCall ;DOS function to change vector
MOV AX,GetVec+DosCall;Get DOS function vector
INT DosCall
MOV WORD PTR [OldInt21], BX
MOV WORD PTR [OldInt21+2],ES
MOV DX, OFFSET NEWINT21
MOV AX, SetVec+DosCall
INT DosCall ; DOS function to change vector
Mov si, Offset BaseName ; pointer to file name proper
Mov di, FileNamePtr ; pointer into buffer
Push ds
Pop es
Mov cx, 12 ; max 12 chars length
Repne Movsb ; copy them!
Mov ax, FileNamePtr ; make FileNamePtr point to
Add ax, 7 ; last digit in name
Mov FileNamePtr, ax
;----------------------------test ----------------------------------
Int 09h
;----------------------------test ----------------------------------
;-----------------------------------------------------------------------
; Deallocate our copy of the environment.
; Leave code and space for the buffer resident.
;-----------------------------------------------------------------------
MOV AX,DS:[002CH] ;Get segment of environment
MOV ES,AX ;Put it into ES
MOV AH,FreeMem ;Release allocated memory
INT DosCall
Mov dx, Offset InstallMsg; tell we have installed
Mov ah, PrintString
Int DosCall
MOV DX,(OFFSET LASTBYTE - OFFSET CSEG + 15)SHR 4
MOV AX,Keep
INT DosCall
; Code for removal of resident part:
Remove: Cmp ax, InstalledCode ; request for removal
Je Remove1 ; if we're there, proceed;
Mov dx, Offset NotThereMsg ; otherwise tell we're not there
Mov al, 3
Jmp ShowMsg
Remove1: Push ds
Mov ax, RemoveCode ; prepare removal
Int 16h ; call our routine
Pop ds ; retrieve data segment address
Mov es, ax ; memory of routine:
Mov ah, FreeMem ; free it!
Int DOSCall
Mov dx, Offset RemovedMsg ; report unloading
Xor al, al
Jmp ShowMsg
; Code for display of hot key:
ShowKey: Mov dx, Offset HitKeyMsg ; Tell we're all set
Mov ah, PrintString
Int DosCall
MOV AX,GetVec+09h ; Get keyboard break vector
INT DosCall
MOV WORD PTR [OldInt09], BX; Save segment
MOV WORD PTR [OldInt09+2],ES; Save offset
MOV DX, OFFSET DummyInt09 ; point to our wee interceptor
MOV AX, SetVec+09h
INT DosCall ; DOS function to change vector
GetHotKey: Xor ah, ah ; Get a proper key
Int 16h
Mov dx, word ptr [cs:OldInt09] ; point back to normal
Mov ax, word ptr [cs:OldInt09+2]
Push ds
Mov ds, ax
Mov ax, SetVec+09h ; Reestablish old INT 09h handler
Int DOSCall
Pop ds
Mov ah, HotKey ; recover hot key code
Mov al, ShiftMask ; ... and shift mask
Call ShowNum ; display that number
Mov ax, 4C00h ; exit with error code 0
Int DosCall
INITIALIZE ENDP
ShowNum Proc Near
; displays ax in hex format
Push ax
Push cx
Push dx
Mov cx, 4 ; 4 hex digits
ShowNum1: Push ax ; push it
Push cx
Mov cl, 4
ShR ax, cl ; shift right one nibble
Pop cx
Loop ShowNum1
; now 4 nibbles are on stack
Mov cx, 4
ShowNum2: Pop dx ; recall next nibble
And dl, 0Fh ; mask out other nibbles
Cmp dl, 9 ; is it above 9?
Jbe ShowNum3
Add dl, 'A'-'0'-10 ; convert to letter A..F
ShowNum3: Add dl, '0' ; convert to digit
Mov ah, PrintChar ; display it
Int DosCall
Loop ShowNum2
Pop dx
Pop cx
Pop ax
Ret
ShowNum EndP
ParseArgs Proc Near
; parse command line arguments; return action code in ah:
; ah=0: install; ah=1: usage; ah=2: remove; ah=3: display hot key
; also sets path string and/or hot key code
Push si
Push di
Mov si, Offset CmdLine + 1 ; point to command line
Xor ah, ah ; init cmd marker
PANext: Lodsb ; get next char
Cmp al, CR ; at end?
Je PADone ; if so, finish
Cmp al, ' ' ; ignore this?
Je PANext
Cmp al, ',' ; ignore this?
Je PANext
Cmp al, Tab ; ignore this?
Je PANext
Cmp al, '/' ; switch char?
Je PASwitch ; skip if so
Cmp al, '-' ; switch char?
Jne PAUsage ; skip if not
PASwitch: Lodsb ; which switch?
Or al, 20h ; convert to lower case
Cmp al, 'u' ; request uninstallation?
Jne PASw3 ; skip if not
Mov ah, 2 ; remember to remove
Jmp Short PANext
PASw3: Cmp al, 'k' ; hot key spec?
Jne PASw4 ; skip if not
Mov bh, ah
Call GetNum ; returns number in ax
Or ax, ax ; hot key help requested?
Je PASw3A ; if so, jot it down!
Mov HotKey, ah
Mov ShiftMask, al
Mov ah, bh
Jmp Short PANext
PASw3A: Mov ah, 3 ; 'hot key help' request
Jmp Short PANext
PASw4: Cmp al, 'p' ; request for outfile path?
Je PASw4A ; if so, proceed to store it
PAUsage: Mov ah, 1 ; otherwise illegal arg
PADone: Pop di
Pop si
Ret
; get path, store it in appropriate buffer:
PASw4A: Mov di, FileNamePtr ; pointer to path buffer
PASw4B: Lodsb ; get next byte
Cmp al, CR ; end of cmd line?
Je PASw4C
Cmp al, ' ' ; end of arg?
Je PASw4C
Cmp al, Tab ; end of arg?
Je PASw4C
Stosb ; else store char in path
Jmp Short PASw4B
PASw4C: Dec si ; decrement cmd line ptr
Cmp byte ptr [di-1], '\' ; does path end in '\'?
Je PASw4D
Cmp byte ptr [di-1], ':' ; does path end in ':'?
Je PASw4D
Mov al, '\' ; else force ending '\'
Stosb
PASw4D: Mov FileNamePtr, di ; update path pointer
Jmp PANext ; and scan on
ParseArgs EndP
GetNum Proc Near
; reads hex number from current position in command line (ds:si),
; returns it in ax
Push bx
Push cx
Xor bx, bx ; assemble number here
Mov cl, 4 ; convenient shift factor
GetNum1: Lodsb ; get next char
Cmp al, CR ; check if end of argument
Je GetNumEnd
Cmp al, ' ' ; ...
Je GetNumEnd
Cmp al, Tab ; ...
Je GetNumEnd
Or al, 20h ; make lowercase
Sub al, '0' ; try to make it a decimal digit
Jc GetNum1 ; was too small; ignore
Cmp al, 9
Jbe GetNum2 ; success!
Sub al, 'a'-'0'+10 ; else, try true hex digit
Jc GetNum1 ; too small; ignore
Cmp al, 15
Ja GetNum1 ; too large; ignore
GetNum2: ShL bx, cl ; shift earlier digits
Or bl, al ; add in new digit
Jmp Short GetNum1
GetNumEnd: Mov ax, bx ; clean up
Dec si ; back up pointer
Pop cx
Pop bx
Ret
GetNum EndP
DummyInt09 PROC FAR
; same as above, except we just get a key and store it away safely
Assume DS:NOTHING, ES:NOTHING
STI ;Allow other interrupts
PUSH AX ;Must save processor state
IN AL,60H ;Get the scan code
Or al, al
Je DummyI09Exit
Mov HotKey, al ; store it as hot key
PUSH DS ;Preserve DS register
MOV AX,BIOS_SEG ;Get BIOS data segment
MOV DS,AX ;Put it in a segment register
Assume DS:BIOS_SEG
MOV AL,KB_FLAG ;Shift flags
AND AL,0FH ; only
Mov ShiftMask, al ;stow flags away
POP DS ;Restore DS register
DummyI09Exit: POP AX ;Restore the processor state
JMP CS:OldInt09 ;Continue with ROM routine
DummyInt09 EndP
BaseName db 'SCN00000.TXT', 0 ; The first filename
Usage db CR, LF, CR, LF
db 'TextCap 2.0 resident text screen capture', CR,LF,CR,LF
db 'Usage: TextCap [args] where args may be', CR, LF
db '/? : this help screen', CR, LF
db '/K<number> : hex code of hot key; default is 4304 for '
db 'Ctrl-F9', CR, LF
db ' (use /K? to find codes for keys!)', CR, LF
db '/P<path> : for screen dumps; default is current '
db 'directory', CR, LF
db '/U : uninstall', CR, LF
db ' no arg installs with default values'
db CR, LF, '$'
LoadedMsg DB CR, LF, "had already been installed.$"
InstallMsg DB CR, LF, "has been installed.$"
RemovedMsg DB CR, LF, "has been uninstalled.$"
NotThereMsg DB CR, LF, "had not been installed.$"
HitKeyMsg DB CR, LF, "Hit the key to check: $"
CSEG ENDS
END START